home *** CD-ROM | disk | FTP | other *** search
Modula Implementation | 1997-04-23 | 22.7 KB | 616 lines | [TEXT/3PRM] |
- implementation module dialogLayout;
-
- // Dialog layout calculations
-
- import StdClass,StdReal,StdInt,StdMisc,StdString,StdBool;
- import commonDef, mac_types, quickdraw, pointer;
- import deltaFont;
- from deltaPicture import DrawFunction, Picture;
-
- :: ItemInfo
- :== ( [(DialogItemId,String)],
- [(DialogItemId,DialogItemId)],
- [(DialogItemId,[(DialogItemId,Bool)])],
- [(DialogItemId,ControlState)] );
- :: DialogInfo
- :== ItemInfo;
-
- :: DialogDef *s *io
- = PropertyDialog DialogId DialogTitle [DialogAttribute] (SetFunction s io)
- (ResetFunction s io) [DialogItem s io]
- | CommandDialog DialogId DialogTitle [DialogAttribute]
- DialogItemId [DialogItem s io]
- | AboutDialog ApplicationName PictureDomain [DrawFunction] (AboutHelpDef s io);
-
- :: DialogId :== Int;
- :: DialogTitle :== String;
- :: DialogAttribute
- = DialogPos Measure Measure
- | DialogSize Measure Measure
- | DialogMargin Measure Measure
- | ItemSpace Measure Measure
- | StandByDialog;
- :: Measure = MM Real | Inch Real | Pixel Int;
-
- :: ApplicationName :== String;
- :: AboutHelpDef *s *io
- = AboutHelp ItemTitle (AboutHelpFunction s io)
- | NoHelp;
- :: AboutHelpFunction *s *io :== s -> *(io -> (s,io));
-
- :: DialogItem *s *io
- = DialogButton DialogItemId ItemPos ItemTitle SelectState
- (ButtonFunction s io)
- | DialogIconButton DialogItemId ItemPos PictureDomain IconLook SelectState
- (ButtonFunction s io)
- | StaticText DialogItemId ItemPos String
- | DynamicText DialogItemId ItemPos TextWidth String
- | EditText DialogItemId ItemPos TextWidth NrEditLines String
- | DialogPopUp DialogItemId ItemPos SelectState DialogItemId
- [RadioItemDef s io]
- | RadioButtons DialogItemId ItemPos RowsOrColumns DialogItemId
- [RadioItemDef s io]
- | CheckBoxes DialogItemId ItemPos RowsOrColumns
- [CheckBoxDef s io]
- | Control DialogItemId ItemPos PictureDomain SelectState
- ControlState ControlLook ControlFeel
- (DialogFunction s io);
-
- :: DialogItemId :== Int;
- :: ItemPos = Left | Center | Right | RightTo DialogItemId
- | Below DialogItemId | XOffset DialogItemId Measure
- | YOffset DialogItemId Measure | XY Measure Measure
- | ItemBox Int Int Int Int;
- :: IconLook :== SelectState -> [DrawFunction];
- :: TextWidth :== Measure;
- :: NrEditLines :== Int;
- :: RowsOrColumns = Rows Int | Columns Int;
-
- :: RadioItemDef *s *io
- = RadioItem DialogItemId ItemTitle SelectState (DialogFunction s io);
- :: CheckBoxDef *s *io
- = CheckBox DialogItemId ItemTitle SelectState MarkState (DialogFunction s io);
-
- :: ControlState = BoolCS Bool | IntCS Int | RealCS Real | StringCS String
- | PairCS ControlState ControlState | ListCS [ControlState];
- :: ControlLook :== SelectState -> ControlState -> [DrawFunction];
- :: ControlFeel :== MouseState -> ControlState -> (ControlState,[DrawFunction]);
-
- :: SetFunction *s *io :== ButtonFunction s io;
- :: ResetFunction *s *io :== ButtonFunction s io;
- :: DialogFunction *s *io
- :== DialogInfo -> (DialogState s io) -> DialogState s io;
- :: ButtonFunction *s *io
- :== DialogInfo -> (s -> *(io -> (s,io)));
-
- :: NoticeDef = Notice [String] NoticeButtonDef [NoticeButtonDef];
- :: NoticeButtonDef = NoticeButton NoticeButtonId ItemTitle;
- :: NoticeButtonId :== Int;
-
- :: *DialogState *s *io
- :== ( !DialogRep s io,
- !Toolbox );
- :: DialogRep *s *io
- :== ( !DialogHandle s io,
- !DialogPtr );
- :: NoticeHandle *s *io
- = NoticeH Rect [DialogItem s io];
- :: DialogHandle *s *io
- = DialogH DialogId DialogTitle DialogMode Rect [PopUpHandle]
- [DialogItem s io] DialogDefInfo;
- :: DialogMode
- = Modal
- | Modeless;
- :: DialogDefInfo
- = DialogRest DialogKind [DialogAttribute] DialogItemId;
- // The last argument is the id of the default button.
- :: DialogKind
- = Property
- | Command;
- :: PopUpHandle
- :== ( !DialogItemId,
- !MacMenuHandle );
-
- :: ItPos
- :== ( !DialogItemId,
- !ItemPos,
- !Rect,
- ![CPos] );
- :: CPos
- :== ( !DialogItemId,
- !Rect );
-
-
- DialogLayoutError :: String String -> .x;
- DialogLayoutError f error = Error f "dialogLayout" error;
-
-
- CreateDialogState :: !(!DialogRep s io, !Toolbox) -> DialogState s io;
- CreateDialogState dState = dState;
-
- UnpackDialogState :: !(DialogState s io) -> (!DialogRep s io, !Toolbox);
- UnpackDialogState dState = dState;
-
- DialogInfoToItemInfo :: !DialogInfo -> ItemInfo;
- DialogInfoToItemInfo dInfo = dInfo;
-
- DialogHandleToDialogInfo :: !(DialogHandle s io) -> DialogInfo;
- DialogHandleToDialogInfo (DialogH _ _ _ _ _ items _) = CreateDialogInfo items;
-
- CreateDialogInfo :: ![DialogItem s io] -> DialogInfo;
- CreateDialogInfo [EditText id ps tw nl text : rest]
- = ([(id,text):edits],radios,checks,ctrls);
- where {
- (edits,radios,checks,ctrls) = CreateDialogInfo rest;
- };
- CreateDialogInfo [DialogPopUp id ps ab di rs : rest]
- = (edits,[(id,di):radios],checks,ctrls);
- where {
- (edits,radios,checks,ctrls) = CreateDialogInfo rest;
- };
- CreateDialogInfo [RadioButtons id ps rc di rs : rest]
- = (edits,[(id,di):radios],checks,ctrls);
- where {
- (edits,radios,checks,ctrls) = CreateDialogInfo rest;
- };
- CreateDialogInfo [CheckBoxes id ps rc boxes : rest]
- = (edits,radios,[(id,CreateCheckBoxesInfo boxes):checks],ctrls);
- where {
- (edits,radios,checks,ctrls) = CreateDialogInfo rest;
- };
- CreateDialogInfo [Control id ps pd ab state cl cf df : rest]
- = (edits,radios,checks,[(id,state):ctrls]);
- where {
- (edits,radios,checks,ctrls) = CreateDialogInfo rest;
- };
- CreateDialogInfo [_ : rest] = CreateDialogInfo rest;
- CreateDialogInfo _ = ([],[],[],[]);
-
- CreateCheckBoxesInfo :: [CheckBoxDef s io] -> [(DialogItemId,Bool)];
- CreateCheckBoxesInfo [CheckBox id _ _ mark _ : rest]
- = [(id,MarkToBool mark) : CreateCheckBoxesInfo rest];
- CreateCheckBoxesInfo _ = [];
-
- MarkToBool :: MarkState -> Bool;
- MarkToBool Mark = True;
- MarkToBool _ = False;
-
-
- MMPerInch :== 25.4;
- LineHeight :== 16; // The line height of the Macintosh dialog font: Plain Chicago 12.
- BaseOfs :== 12; // Ascent+Leading of the Macintosh dialog font.
- MinButWid :== 55;
- ButHgt :== 20;
- RadBoxWid :== 32;
- PopUpWid :== 24;
- DummyItPos :== (0,Left,(0,0,0,0),[]);
-
-
- /* Calculate the precise position (in pixels) of each dialog item. */
-
- CalcItemBoxes :: !(!Int,!Int) !(!Int,!Int) ![DialogItem s io] -> (!Int,!Int,![DialogItem s io]);
- CalcItemBoxes margins=:(hmg,vmg) spaces=:(hsp,vsp) items
- = (width, hgt + vmg, AddItemBoxes pos3 items);
- where {
- pos1 = CalcItemSizes DialogFont items;
- width = wid + hmg;
- (wid,hgt,pos2) = CalcItemPositions hmg (vmg - vsp) margins spaces pos1 [];
- pos3 = RenterItems width hmg pos2 [];
- };
-
- /* Calculate the width and height of each item. */
-
- CalcItemSizes :: !Font ![DialogItem s io] -> [ItPos];
- CalcItemSizes dfont [DialogButton id pos txt _ _ : items]
- = [(id,pos,CalcButtonSize dfont pos txt,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [DialogIconButton id pos pd _ _ _ : items]
- = [(id,pos,CalcUserDefSize pos pd,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [StaticText id pos txt : items]
- = [(id,pos,CalcStaticTextSize dfont pos txt,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [DynamicText id pos wid _ : items]
- = [(id,pos,CalcEditTextSize pos wid 1,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [EditText id pos wid nrl _ : items]
- = [(id,pos,CalcEditTextSize pos wid nrl,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [DialogPopUp id pos _ _ buts : items]
- = [(id,pos,CalcPopUpSize dfont pos buts,[]) : CalcItemSizes dfont items];
- CalcItemSizes dfont [RadioButtons id pos roc _ buts : items]
- = [(id,pos,CalcRadioBoxSize pos roc nr maxw,[]) : CalcItemSizes dfont items];
- where {
- (nr,maxw) = RadioButtonsNr_and_MaxWidth dfont 0 0 buts;
- };
- CalcItemSizes dfont [CheckBoxes id pos roc boxes : items]
- = [(id,pos,CalcRadioBoxSize pos roc nr maxw,[]) : CalcItemSizes dfont items];
- where {
- (nr,maxw) = CheckBoxesNr_and_MaxWidth dfont 0 0 boxes;
- };
- CalcItemSizes dfont [Control id pos pd _ _ _ _ _ : items]
- = [(id,pos,CalcUserDefSize pos pd,[]) : CalcItemSizes dfont items];
- CalcItemSizes _ [] = [];
- CalcItemSizes _ _
- = DialogLayoutError "CalcItemSizes" "Unknown dialog item";
-
- CalcButtonSize :: !Font !ItemPos !String -> Rect;
- CalcButtonSize dfont (ItemBox l t w h) _ = ProperRect (l,t,w,h);
- CalcButtonSize dfont _ title = (0,0,bwid,ButHgt);
- where {
- bwid = Max MinButWid (12 + FontStringWidth title dfont);
- };
-
- CalcUserDefSize :: !ItemPos !PictureDomain -> Rect;
- CalcUserDefSize (ItemBox l t w h) _ = ProperRect (l,t,w,h);
- CalcUserDefSize pos ((l,t),(r,b)) = (0,0,ABS (r - l),ABS (b - t));
-
- CalcStaticTextSize :: !Font !ItemPos !String -> Rect;
- CalcStaticTextSize _ (ItemBox l t w h) _ = ProperRect (l,t,w,h);
- CalcStaticTextSize dfont pos text = (0,0,4 + FontStringWidth text dfont,LineHeight);
-
- CalcEditTextSize :: !ItemPos !Measure !Int -> Rect;
- CalcEditTextSize (ItemBox l t w h) _ _ = ProperRect (l,t,w,h);
- CalcEditTextSize _ wid nrl = (0,0,HorMeasureToPixels wid,nrl * LineHeight);
-
- CalcPopUpSize :: !Font !ItemPos ![RadioItemDef s io] -> Rect;
- CalcPopUpSize _ (ItemBox l t w h) _ = ProperRect (l,t,w,h);
- CalcPopUpSize dfont _ buts = (0,0,PopUpWid + bwid,LineHeight);
- where {
- (nr,bwid) = RadioButtonsNr_and_MaxWidth dfont 0 0 buts;
- };
-
- CalcRadioBoxSize :: !ItemPos !RowsOrColumns !Int !Int -> Rect;
- CalcRadioBoxSize (ItemBox l t w h) (Rows nr) nb _
- = ProperRect (l,t,w * UpDiv nb nr, h * nr);
- CalcRadioBoxSize (ItemBox l t w h) (Columns nc) nb _
- = ProperRect (l,t,w * nc,h * UpDiv nb nc);
- CalcRadioBoxSize pos (Rows nr) nb wid
- = (0,0,(wid + RadBoxWid) * UpDiv nb nr, LineHeight * nr);
- CalcRadioBoxSize pos (Columns nc) nb wid
- = (0,0,(wid + RadBoxWid) * nc,LineHeight * UpDiv nb nc);
-
- RadioButtonsNr_and_MaxWidth :: !Font !Int !Int ![RadioItemDef s io] -> (!Int,!Int);
- RadioButtonsNr_and_MaxWidth dfont nr maxw [RadioItem _ text _ _ : rest]
- = RadioButtonsNr_and_MaxWidth dfont (inc nr) maxw` rest;
- where {
- maxw` = Max maxw (FontStringWidth text dfont);
- };
- RadioButtonsNr_and_MaxWidth _ nr maxw _ = (nr,maxw);
-
- CheckBoxesNr_and_MaxWidth :: !Font !Int !Int ![CheckBoxDef s io] -> (!Int,!Int);
- CheckBoxesNr_and_MaxWidth dfont nr maxw [CheckBox _ text _ _ _ : rest]
- = CheckBoxesNr_and_MaxWidth dfont (inc nr) maxw` rest;
- where {
- maxw` = Max maxw (FontStringWidth text dfont);
- };
- CheckBoxesNr_and_MaxWidth _ nr maxw _ = (nr,maxw);
-
- ProperRect :: !Rect -> Rect;
- ProperRect (l,t,w,h) = (ABS l, ABS t, ABS w, ABS h);
-
- UpDiv :: !Int !Int -> Int;
- UpDiv a b
- | b == 0 = a;
- | a mod b == 0 = a/b;
- = inc (a/b);
-
- Div :: !Int !Int -> Int;
- Div a b
- | b == 0 = a;
- = a/b;
-
- /* After calculating width and height of each item the positions can be determined.
- On the fly the width and height of the dialog are calculated.
- (NB: Renter = Right or Center)
- */
- CalcItemPositions :: !Int !Int !(!Int,!Int) !(!Int,!Int) ![ItPos] ![ItPos] -> (!Int,!Int,![ItPos]);
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [(id,Left,(l,t,w,h),ci):rest] poss
- = CalcItemPositions maxx` (t` + h) mg sp rest [(id,Left,(hm,t`,w,h),ci):poss];
- where {
- maxx` = Max maxx (hm + w);
- t`=: maxy + vs;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [(id,Center,(l,t,w,h),ci):rest] poss
- = CalcItemPositions maxx` (t` + h) mg sp rest [(id,Center,(hm,t`,w,h),ci):poss];
- where {
- maxx` = Max maxx (hm + w);
- t`=: maxy + vs;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [(id,Right,(l,t,w,h),ci):rest] poss
- = CalcItemPositions maxx` (t` + h) mg sp rest [(id,Right,(hm,t`,w,h),ci):poss];
- where {
- maxx` = Max maxx (hm + w); t`=: maxy + vs;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [item1=:(id,RightTo ri,rc,ci):rest] poss
- | exists = CalcItemPositions maxx1 maxy1 mg sp rest (Concat items poss`);
- = CalcItemPositions maxx2 (t` + h) mg sp rest [(id,Left,(hm,t`,w,h),ci):poss];
- where {
- (maxx1,maxy1,items) = PositionRightTo maxx maxy hs ri item1 item2;
- (exists,item2,poss`)= RemoveItPos ri poss;
- maxx2 = Max maxx (hm + w); t` = maxy + vs; (l,t,w,h) = rc;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [item1=:(id,XOffset ri ofs,rc,ci):rest] poss
- | exists = CalcItemPositions maxx1 maxy1 mg sp rest (Concat items poss`);
- = CalcItemPositions maxx2 (t` + h) mg sp rest [(id,Left,(hm,t`,w,h),ci):poss];
- where {
- (maxx1,maxy1,items) = PositionRightTo maxx maxy (HorMeasureToPixels ofs) ri item1 item2;
- (exists,item2,poss`)= RemoveItPos ri poss;
- maxx2 = Max maxx (hm + w); t` = maxy + vs; (l,t,w,h) = rc;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [item1=:(id,Below ri,rc,ci):rest] poss
- | exists = CalcItemPositions maxx1 maxy1 mg sp rest [bpos,item2:poss`];
- = CalcItemPositions maxx2 (t` + h) mg sp rest [(id,Left,(hm,t`,w,h),ci):poss];
- where {
- (maxx1,maxy1,bpos) = PositionBelow maxx maxy vs hm item1 item2;
- (exists,item2,poss`)= RemoveItPos ri poss;
- maxx2 = Max maxx (hm + w); t` = maxy + vs; (l,t,w,h) = rc;
- };
- CalcItemPositions maxx maxy mg=:(hm,vm) sp=:(hs,vs) [item1=:(id,YOffset ri ofs,rc,ci):rest] poss
- | exists = CalcItemPositions maxx1 maxy1 mg sp rest [bpos,item2:poss`];
- = CalcItemPositions maxx2 (t` + h) mg sp rest [(id,Left,(hm,t`,w,h),ci):poss];
- where {
- (maxx1,maxy1,bpos) = PositionBelow maxx maxy (VerMeasureToPixels ofs) hm item1 item2;
- (exists,item2,poss`)= RemoveItPos ri poss;
- maxx2 = Max maxx (hm + w); t` = maxy + vs; (l,t,w,h) = rc;
- };
- CalcItemPositions maxx maxy mg sp [(id,ps=:XY x y,(l,t,w,h),ci):rest] poss
- = CalcItemPositions maxx` maxy` mg sp rest [(id,ps,(l`,t`,w,h),ci):poss];
- where {
- maxx` = Max maxx (l` + w); maxy` = Max maxx (t` + h);
- l` = HorMeasureToPixels x; t` = VerMeasureToPixels y;
- };
- CalcItemPositions maxx maxy mg sp [pos=:(id,ps=:ItemBox l t w h,rc,ci):rest] poss
- = CalcItemPositions (Max maxx (l + w)) (Max maxy (t + h)) mg sp rest [pos:poss];
- CalcItemPositions maxx maxy mg sp [] poss = (maxx,maxy,poss);
-
- PositionRightTo :: !Int !Int !Int !Int !ItPos !ItPos -> (!Int,!Int,![ItPos]);
- PositionRightTo maxx maxy ofs id item1=:(i1,p1,r1,c1) (i2,Center,r2,poss)
- | id == i2 = (mx1,my1,[(i2,Center,r2,[(i1,(l1,t2,w1,h1)):poss])]);
- = (mx2,my2,[(i2,Center,r2,poss`)]);
- where {
- mx1 = Max maxx (l1 + w1); my1 = Max maxy (t2 + h1);
- l1 = l2+w2+ofs; (ld,td,w1,h1) = r1; (l2,t2,w2,h2) = r2;
- (mx2,my2,poss`) = RightToRenter maxx maxy ofs id item1 poss;
- };
- PositionRightTo maxx maxy ofs id item1=:(i1,p1,r1,c1) (i2,Right,r2,poss)
- | id == i2 = (mx1,my1,[(i2,Right,r2,[(i1,(l1,t2,w1,h1)):poss])]);
- = (mx2,my2,[(i2,Right,r2,poss`)]);
- where {
- mx1 = Max maxx (l1 + w1); my1 = Max maxy (t2 + h1);
- l1 = l2+w2+ofs; (ld,td,w1,h1) = r1; (l2,t2,w2,h2) = r2;
- (mx2,my2,poss`) = RightToRenter maxx maxy ofs id item1 poss;
- };
- PositionRightTo maxx maxy ofs id (i1,p1,(ld,td,w1,h1),c1) item2=:(i2,p2,(l2,t2,w2,h2),c2)
- = (mx`,my`,[(i1,p1,(l1,t2,w1,h1),c1),item2]);
- where {
- mx` = Max maxx (l1 + w1); my` = Max maxy (t2 + h1); l1 = l2+w2+ofs;
- };
-
- RightToRenter :: !Int !Int !Int !Int !ItPos ![CPos] -> (!Int,!Int,![CPos]);
- RightToRenter maxx maxy ofs id ipos [cpos=:(ic,rc):rest]
- | id <> ic = (mx1,my1,[cpos : rest`]);
- = (mx2,my2,[cpos, (i1,(l1,t2,w1,h1)) : rest]);
- where {
- (mx1,my1,rest`) = RightToRenter maxx maxy ofs id ipos rest;
- mx2 = Max maxx (l1 + w1); my2 = Max maxy (t2 + h1);
- l1 = l2+w2+ofs; (ld,td,w1,h1) = r1; (l2,t2,w2,h2) = rc;
- (i1,ps,r1,c1) = ipos;
- };
-
- PositionBelow :: !Int !Int !Int !Int !ItPos !ItPos -> (!Int,!Int,!ItPos);
- PositionBelow maxx maxy ofs hmg item1=:(i1,p1,r1,c1) (i2,Center,r2,poss)
- = (mx`,my`,(i1,Center,(hmg,t1,w1,h1),c1));
- where {
- mx` = Max maxx (hmg + w1); my` = Max maxy (t1 + h1);
- t1 = t2+h2+ofs; (ld,td,w1,h1) = r1; (l2,t2,w2,h2) = r2;
- };
- PositionBelow maxx maxy ofs hmg item1=:(i1,p1,r1,c1) (i2,Right,r2,poss)
- = (mx`,my`,(i1,Right,(hmg,t1,w1,h1),c1));
- where {
- mx` = Max maxx (hmg + w1); my` = Max maxy (t1 + h1);
- t1 = t2+h2+ofs; (ld,td,w1,h1) = r1; (l2,t2,w2,h2) = r2;
- };
- PositionBelow maxx maxy ofs hmg (i1,p1,(ld,td,w1,h1),c1) item2=:(i2,p2,(l2,t2,w2,h2),c2)
- = (mx`,my`,(i1,p1,(l2,t1,w1,h1),c1));
- where {
- mx` = Max maxx (l2 + w1); my` = Max maxy (t1 + h1); t1 = t2+h2+ofs;
- };
-
- RemoveItPos :: !Int ![ItPos] -> (!Bool,!ItPos,![ItPos]);
- RemoveItPos rid [ip=:(iid,Center,r,cits):rest]
- | rid <> iid && not (ItPosInRenterList rid cits) = (exists,pos,[ip:rest`]);
- = (True,ip,rest);
- where {
- (exists,pos,rest`) = RemoveItPos rid rest;
- };
- RemoveItPos rid [ip=:(iid,Right,r,cits):rest]
- | rid <> iid && not (ItPosInRenterList rid cits) = (exists,pos,[ip:rest`]);
- = (True,ip,rest);
- where {
- (exists,pos,rest`) = RemoveItPos rid rest;
- };
- RemoveItPos rid [ip=:(iid,p,r,c):rest]
- | rid <> iid = (exists,pos,[ip:rest`]);
- = (True,ip,rest);
- where {
- (exists,pos,rest`) = RemoveItPos rid rest;
- };
- RemoveItPos _ [] = (False,DummyItPos,[]);
-
- ItPosInRenterList :: !Int ![CPos] -> Bool;
- ItPosInRenterList iid [(cid,r):rest] | iid == cid = True;
- = ItPosInRenterList iid rest;
- ItPosInRenterList _ [] = False;
-
-
- /* After positioning the items the Center/Right items must be repositioned
- according to the width of the dialog retrieved in the previous pass. */
-
- RenterItems :: !Int !Int ![ItPos] ![ItPos] -> [ItPos];
- RenterItems wid hmg [(id,Center,(l,t,w,h),cits):rest] poss
- = RenterItems wid hmg rest [(id,Center,(l + delta,t,w,h),cits`):poss];
- where {
- cits` = ShiftRenterItems delta cits;
- delta = (wid - (RenterItemsMaxX (l + w) cits + hmg))/2;
- };
- RenterItems wid hmg [(id,Right,(l,t,w,h),cits):rest] poss
- = RenterItems wid hmg rest [(id,Right,(l + delta,t,w,h),cits`):poss];
- where {
- cits` = ShiftRenterItems delta cits;
- delta = wid - (RenterItemsMaxX (l + w) cits + hmg);
- };
- RenterItems wid hmg [item:rest] poss
- = RenterItems wid hmg rest [item:poss];
- RenterItems _ _ [] poss = poss;
-
- ShiftRenterItems :: !Int ![CPos] -> [CPos];
- ShiftRenterItems delta [(id,(l,t,w,h)):rest]
- = [(id,(l + delta,t,w,h)) : ShiftRenterItems delta rest];
- ShiftRenterItems _ [] = [];
-
- RenterItemsMaxX :: !Int ![CPos] -> Int;
- RenterItemsMaxX max [(id,(l,t,w,h)):rest] = RenterItemsMaxX (Max max (l + w)) rest;
- RenterItemsMaxX max [] = max;
-
-
- /* After positioning/rentering the items the list of Rects must be transformed to
- ItemBoxes and added to the original list of items. This routine also checks
- whether the default id of RadioButtons or a DialogPopUps really exist. If not,
- the first RadioItem in the list is chosen to be the initially marked item. */
-
- AddItemBoxes :: ![ItPos] ![DialogItem s io] -> [DialogItem s io];
- AddItemBoxes poss [DialogButton id pos txt s f : items]
- = [DialogButton id ibox txt s f : AddItemBoxes poss` items];
- where {
- (ibox,poss`) = GetItemPosition id poss;
- };
- AddItemBoxes poss [DialogIconButton id pos pd l s f : items]
- = [DialogIconButton id ibox pd l s f : AddItemBoxes poss` items];
- where {
- (ibox,poss`) = GetItemPosition id poss;
- };
- AddItemBoxes poss [StaticText id pos txt : items]
- = [StaticText id ibox txt : AddItemBoxes poss` items];
- where {
- (ibox,poss`) = GetItemPosition id poss;
- };
- AddItemBoxes poss [DynamicText id pos wid txt : items]
- = [DynamicText id ibox wid txt : AddItemBoxes poss` items];
- where {
- (ibox,poss`) = GetItemPosition id poss;
- };
- AddItemBoxes poss [EditText id pos wid nrl t : items]
- = [EditText id ibox wid nrl t : AddItemBoxes poss` items];
- where {
- (ibox,poss`) = GetItemPosition id poss;
- };
- AddItemBoxes poss [DialogPopUp id pos ab di buts : items]
- = [DialogPopUp id ibox ab di` buts : AddItemBoxes poss` items];
- where {
- (ibox,poss`)= GetItemPosition id poss;
- di` = CheckDefaultRadioItemId di buts;
- };
- AddItemBoxes poss [RadioButtons id pos roc di buts : items]
- = [RadioButtons id ibox` roc di` buts : AddItemBoxes poss` items];
- where {
- ibox` = RadioBoxItemBox (Length_new buts) roc ibox;
- (ibox,poss`)= GetItemPosition id poss;
- di` = CheckDefaultRadioItemId di buts;
- };
- AddItemBoxes poss [CheckBoxes id pos roc boxes : items]
- = [CheckBoxes id ibox` roc boxes : AddItemBoxes poss` items];
- where {
- ibox` = RadioBoxItemBox (Length_new boxes) roc ibox;
- (ibox,poss`)= GetItemPosition id poss;
- };
- AddItemBoxes poss [Control id pos pd a s l f d : items]
- = [Control id ibox pd a s l f d : AddItemBoxes poss` items];
- where {
- (ibox,poss`)= GetItemPosition id poss;
- };
- AddItemBoxes _ [] = [];
-
- GetItemPosition :: !Int ![ItPos] -> (!ItemPos,![ItPos]);
- GetItemPosition iid poss=:[pos=:(pid,ps=:Center,rect,cits):rest]
- | iid == pid = (ItemBox l t w h,poss);
- | inclist = (ibox,[(pid,ps,rect,cits`):rest]);
- = ( box,[pos:rest`]);
- where {
- (inclist,ibox,cits`)= FindItemBoxInRenterList iid cits;
- (box,rest`) = GetItemPosition iid rest;
- (l,t,w,h) = rect;
- };
- GetItemPosition iid poss=:[pos=:(pid,ps=:Right,rect,cits):rest]
- | iid == pid = (ItemBox l t w h,poss);
- | inclist = (ibox,[(pid,ps,rect,cits`):rest]);
- = (box,[pos:rest`]);
- where {
- (inclist,ibox,cits`)= FindItemBoxInRenterList iid cits;
- (box,rest`) = GetItemPosition iid rest;
- (l,t,w,h) = rect;
- };
- GetItemPosition iid [pos=:(pid,ps,rect,cits):rest]
- | iid == pid = (ItemBox l t w h, rest);
- = (box,[pos:rest`]);
- where {
- (box,rest`) = GetItemPosition iid rest;
- (l,t,w,h) = rect;
- };
- GetItemPosition _ []
- = DialogLayoutError "GetItemPosition" "Unknown item id";
-
- FindItemBoxInRenterList :: !Int ![CPos] -> (!Bool,!ItemPos,![CPos]);
- FindItemBoxInRenterList iid [cpos=:(cid,rect):rest]
- | iid == cid = (True,ItemBox l t w h,rest);
- = (found,box,[cpos:rest`]);
- where {
- (found,box,rest`) = FindItemBoxInRenterList iid rest;
- (l,t,w,h) = rect;
- };
- FindItemBoxInRenterList _ rest = (False,Left,rest);
-
- RadioBoxItemBox :: !Int !RowsOrColumns !ItemPos -> ItemPos;
- RadioBoxItemBox nrb (Rows nr) (ItemBox l t w h) = ItemBox l t (Div w (UpDiv nrb nr)) (Div h nr);
- RadioBoxItemBox nrb (Columns nc) (ItemBox l t w h) = ItemBox l t (Div w nc) (Div h (UpDiv nrb nc));
-
- CheckDefaultRadioItemId :: !DialogItemId ![RadioItemDef s io] -> DialogItemId;
- CheckDefaultRadioItemId did items=:[RadioItem fid tt ab df : rest]
- = CheckDefRadioItemId fid did items;
- CheckDefaultRadioItemId did []
- = DialogLayoutError "in dialog definition" "empty list of RadioItems";
-
- CheckDefRadioItemId :: !DialogItemId !DialogItemId ![RadioItemDef s io] -> DialogItemId;
- CheckDefRadioItemId fid did [RadioItem id tt ab df : rest]
- | id == did = did;
- = CheckDefRadioItemId fid did rest;
- CheckDefRadioItemId fid _ _ = fid;
-
-
- // DialogFont returns the standard dialog font: Chicago 12.
-
- DialogFont :: Font;
- DialogFont = font;
- where {
- (_,font) = SelectFont "Chicago" [] 12;
- };
-
- // Calculations from Measures (inches, millimeters or pixels) to screen pixels.
-
- HorMeasureToPixels :: !Measure -> Int;
- HorMeasureToPixels (Pixel p) = ABS p;
- HorMeasureToPixels (Inch i) = InchesToHPixels (ABSR i);
- HorMeasureToPixels (MM m) = InchesToHPixels (ABSR m / MMPerInch);
-
- VerMeasureToPixels :: !Measure -> Int;
- VerMeasureToPixels (Pixel p) = ABS p;
- VerMeasureToPixels (Inch i) = InchesToVPixels (ABSR i);
- VerMeasureToPixels (MM m) = InchesToVPixels (ABSR m / MMPerInch);
-
- InchesToHPixels :: !Real -> Int;
- InchesToHPixels i = toInt (i * toReal hRes);
- where {
- (hRes,_) = LoadWord ScrnHResAddress NewToolbox;
- };
-
- InchesToVPixels :: !Real -> Int;
- InchesToVPixels i = toInt (i * toReal vRes);
- where {
- (vRes,_) = LoadWord ScrnVResAddress NewToolbox;
- };
-